home *** CD-ROM | disk | FTP | other *** search
- ; PC/FTP Packet Driver source, conforming to version 1.05 of the spec
- ; Russell Nelson, Clarkson University. July 20, 1988
- ; Updated to version 1.08 Feb. 17, 1989.
- ; Copyright 1988,1989 Russell Nelson
-
- ; This program is free software; you can redistribute it and/or modify
- ; it under the terms of the GNU General Public License as published by
- ; the Free Software Foundation, version 1.
- ;
- ; This program is distributed in the hope that it will be useful,
- ; but WITHOUT ANY WARRANTY; without even the implied warranty of
- ; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
- ; GNU General Public License for more details.
- ;
- ; You should have received a copy of the GNU General Public License
- ; along with this program; if not, write to the Free Software
- ; Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
-
- include defs.asm
-
- code segment byte public
- assume cs:code, ds:code
-
- extrn phd_dioa: byte
- extrn phd_environ: word
-
- ;usage_msg is of the form "usage: driver <packet_int_no> <args>"
- extrn usage_msg: byte
-
- ;copyright_msg is of the form:
- ;"Packet driver for the foobar",CR,LF
- ;"Portions Copyright 19xx, J. Random Hacker".
- extrn copyright_msg: byte
-
- copyleft_msg label byte
- db "Packet driver skeleton copyright 1988-89, Russell Nelson.",CR,LF
- db "This program is free software; see the file COPYING for details.",CR,LF
- db "NO WARRANTY; see the file COPYING for details.",CR,LF
- crlf_msg db CR,LF,'$'
-
- ;parse_args should parse the arguments.
- ;called with ds:si -> immediately after the packet_int_no.
- extrn parse_args: near
-
- extrn our_isr: near, their_isr: dword
- extrn packet_int_no: byte
- extrn is_at: byte, sys_features: byte
- extrn int_no: byte
- extrn driver_class: byte
-
- location_msg db "Packet driver loaded at segment ",'$'
-
- packet_int_no_name db "Packet interrupt number ",'$'
- eaddr_msg db "My Ethernet address is ",'$'
-
- signature db 'PKT DRVR',0
- signature_len equ $-signature
-
- already_msg db CR,LF,"There is already a packet driver at ",'$'
- packet_int_msg db CR,LF
- db "Error: <packet_int_no> should be in the range 0x60 to 0x80"
- db '$'
- int_msg db CR,LF
- db "Error: <int_no> should be no larger than "
- int_msg_num label word
- db "xx"
- db '$'
-
- our_address db EADDR_LEN dup(?)
- public etopen_diagn
- etopen_diagn db 0 ; errorlevel from etopen if set
-
- ;etopen should initialize the device. If it needs to give an error, it
- ;can issue the error message and quit to dos.
- extrn etopen: near
-
- ;get the address of the interface.
- ;enter with es:di -> place to get the address, cx = size of address buffer.
- ;exit with nc, cx = actual size of address, or cy if buffer not big enough.
- extrn get_address: near
-
- already_error:
- mov dx,offset already_msg
- mov di,offset packet_int_no
- call print_number
- mov ax,4c05h ; give errorlevel 5
- int 21h
-
- usage_error:
- mov dx,offset usage_msg
- error:
- mov ah,9
- int 21h
- mov ax,4c0ah ; give errorlevel 10
- int 21h
-
- public start_1
- start_1:
- mov dx,offset copyright_msg
- mov ah,9
- int 21h
-
- mov dx,offset copyleft_msg
- mov ah,9
- int 21h
-
- mov si,offset phd_dioa+1
- cmp byte ptr [si],CR ;end of line?
- je usage_error
-
- ;print the location we were loaded at.
- mov dx,offset location_msg
- mov ah,9
- int 21h
-
- mov ax,cs ;print cs as a word.
- call wordout
-
- mov dx,offset crlf_msg
- mov ah,9
- int 21h
-
- mov di,offset packet_int_no ;parse the packet interrupt number
- mov bx,offset packet_int_no_name
- call get_number ; for them.
-
- call parse_args
-
- cmp byte ptr [si],CR ;end of line?
- jne usage_error
-
- mov dx,offset packet_int_msg;make sure that the packet interrupt
- cmp packet_int_no,60h ; number is in range.
- jb error
- cmp packet_int_no,80h
- ja error
-
- mov ah,35h ;get their packet interrupt.
- mov al,packet_int_no
- int 21h
-
- lea di,3[bx] ;see if there is already a signature
- mov si,offset signature ; there.
- mov cx,signature_len
- repe cmpsb
- je already_error ;yes, so we can't go there.
-
- mov ah,0c0h
- int 15h ; es:bx <- sys features block
- jc old_bios
- add bx,5
- mov al,es:[bx] ; get system feature byte
- mov sys_features,al
- test sys_features,40h ; 2nd 8259?
- jnz two_8259s
- old_bios:
- mov ax,0f000h ;ROM segment
- mov es,ax
- mov al,7 ;maximum interrupt on a PC
- mov int_msg_num,'7'+' '*256
- cmp word ptr es:[0fffeh],0fch ;is this an AT?
- jne not_at ;no.
- two_8259s:
- mov al,15 ;maximum interrupt on an AT
- mov int_msg_num,'1'+'5'*256
-
- inc is_at ;yes - remember that we've got an AT.
- or sys_features,40h ; ATs have a 2nd 8259
- cmp int_no,2 ;map IRQ 2 to IRQ 9.
- jne not_at
- mov int_no,9
- not_at:
-
- mov dx,offset int_msg ;make sure that the packet interrupt
- cmp int_no,al ; number is in range.
- jbe int_ok
- jmp error
- int_ok:
-
- call etopen ;init the driver. If any errors,
- ;this routine returns cy.
- jc no_resident
-
- push dx ;remember where they want to end.
-
- mov ah,35h ;remember their packet interrupt.
- mov al,packet_int_no
- int 21h
- mov their_isr.offs,bx
- mov their_isr.segm,es
-
- mov ah,25h ;install our packet interrupt
- mov dx,offset our_isr
- int 21h
-
- cmp driver_class,1 ;Ethernet?
- jne print_addr_2 ;no, don't print what we don't have.
-
- push ds
- pop es
- mov di,offset our_address
- mov cx,EADDR_LEN
- call get_address
-
- mov dx,offset eaddr_msg
- mov ah,9
- int 21h
-
- mov cx,EADDR_LEN
- mov si,offset our_address
- print_addr:
- push cx
- lodsb
- mov cl,' ' ;Don't eliminate leading zeroes.
- call byteout
- pop cx
- cmp cx,1
- je print_addr_1
- mov al,':'
- call chrout
- print_addr_1:
- loop print_addr
-
- mov dx,offset crlf_msg ;can't depend on DOS to newline for us.
- mov ah,9
- int 21h
-
- print_addr_2:
-
- mov ah,49h ;free our environment, because
- mov es,phd_environ ; we won't need it.
- int 21h
-
- mov bx,1 ;get the stdout handle.
- mov ah,3eh ;close it in case they redirected it.
- int 21h
-
- pop dx ;get their ending address.
- add dx,0fh ;round up to next highest paragraph.
- mov cl,4
- shr dx,cl
- mov ah,31h ;terminate, stay resident.
- mov al,etopen_diagn ; errorlevel (0 - 9, just diagnostics)
- int 21h
-
- no_resident:
- mov ax,4c00h + 32 ; give errorlevel 32
- cmp al,etopen_diagn
- ja no_et_diagn ; etopen gave specific reason?
- mov al,etopen_diagn ; yes, use that for error level
- no_et_diagn:
- int 21h
-
- ; Suggested errorlevels:
- ;
- ; _____________________ 0 = normal
- ; 1 = unsuitable memory address given; corrected
- ; In most cases every- 2 = unsuitable IRQ level given; corrected
- ; thing should work as 3 = unsuitable DMA channel given; corrected
- ; expected for lev 1-5 4 = unsuitable IO addr given; corrected (only 1 card)
- ; _____________________ 5 = packet driver for this int # already loaded
- ; External errors, when 20 = general cable failure (but pkt driver is loaded)
- ; corrected normal 21 = network cable is open -"-
- ; operation starts 22 = network cable is shorted -"-
- ; _____________________ 23 =
- ; Packet driver not 30 = usage message
- ; loaded. A new load 31 = arguments out of range
- ; attempt must be done 32 = unspecified device initialization error
- ; 33 =
- ; 34 = suggested memory already occupied
- ; 35 = suggested IRQ already occupied
- ; 36 = suggested DMA channel already occupied
- ; 37 = could not find the network card at this IO address
-
- public get_number
- get_number:
- mov bp,10 ;we default to 10.
- jmp short get_number_0
-
- public get_hex
- get_hex:
- mov bp,16
- ;get a hex number, skipping leading blanks.
- ;enter with si->string of digits,
- ; bx -> dollar terminated name of number,
- ; di -> dword to store the number in. [di] is not modified if no
- ; digits are given, so it acts as the default.
- ;return cy if there are no digits at all.
- ;return nc, bx:cx = number, and store bx:cx at [di].
- get_number_0:
- push bx ;remember the name of this number.
- call skip_blanks
- call get_digit ;is there really a number here?
- jc get_number_3
- or al,al ;Does the number begin with zero?
- jne get_number_4 ;no.
- mov bp,8 ;yes - they want octal.
- get_number_4:
-
- xor cx,cx ;get a hex number.
- xor bx,bx
- get_number_1:
- lodsb
- cmp al,'x' ;did they really want hex?
- je get_number_5 ;yes.
- cmp al,'X' ;did they really want hex?
- je get_number_5 ;yes.
- call get_digit ;convert a character into an int.
- jc get_number_2 ;not a digit (neither hex nor dec).
- xor ah,ah
- cmp ax,bp ;larger than our base?
- jae get_number_2 ;yes.
-
- push ax ;save the new digit.
-
- mov ax,bp ;multiply the low word by ten.
- mul cx
- mov cx,ax ;keep the low word.
- push dx ;save the high word for later.
- mov ax,bp
- mul bx
- mov bx,ax ;we keep only the low word (which is our high word)
- pop dx
- add bx,ax ;add the high result from earlier.
-
- pop ax ;get the new digit back.
- add cx,ax ;add the new digit in.
- adc bx,0
- jmp get_number_1
- get_number_5:
- mov bp,16 ;change the base to hex.
- jmp get_number_1
- get_number_2:
- dec si
- mov [di],cx ;store the parsed number.
- mov [di+2],bx
- clc
- jmp short get_number_6
- get_number_3:
- mov cx,-1
- mov bx,-1
- cmp al,'?' ;did they ask for the default?
- je get_number_2 ;yes - give them -1.
- stc
- get_number_6:
- pop dx ;get the name of the number back.
-
- pushf ;save some stuff.
- push bx
- push cx
- push si
- push di
- call print_number
- pop di
- pop si
- pop cx
- pop bx
- popf
- ret
-
-
- print_number:
- ;enter with dx -> dollar terminated name of number, di ->dword.
- ;exit with the number printed and the cursor advanced to the next line.
- mov ah,9 ;print the name of the number.
- int 21h
- mov al,'0'
- call chrout
- mov al,'x'
- call chrout
- mov ax,[di] ;print the number in hex.
- mov dx,[di+2]
- call hexout
- mov al,' '
- call chrout
- mov al,'('
- call chrout
- mov ax,[di] ;print the number in decimal.
- mov dx,[di+2]
- call decout
- mov al,')'
- call chrout
- mov al,CR
- call chrout
- mov al,LF
- call chrout
- ret
-
-
- public skip_blanks
- skip_blanks:
- lodsb ;skip blanks.
- cmp al,' '
- je skip_blanks
- cmp al,HT
- je skip_blanks
- dec si
- ret
-
-
- get_digit:
- ;enter with al = character
- ;return nc, al=digit, or cy if not a digit.
- cmp al,'0' ;decimal digit?
- jb get_digit_1 ;no.
- cmp al,'9' ;. .?
- ja get_digit_2 ;no.
- sub al,'0'
- clc
- ret
- get_digit_2:
- or al,20h
- cmp al,'a' ;hex digit?
- jb get_digit_1
- cmp al,'f' ;hex digit?
- ja get_digit_1
- sub al,'a'-10
- clc
- ret
- get_digit_1:
- stc
- ret
-
-
- public hexout
- hexout:
- mov cl,'0' ;prepare to eliminate leading zeroes.
- xchg ax,dx ;just output 32 bits in hex.
- call wordout ;output dx.
- xchg ax,dx
- jmp wordout ;output ax.
-
-
- public decout
- decout:
- mov si,ax ;get the number where we want it.
- mov di,dx
- or ax,dx ;is the number zero?
- jne decout_nonzero
- mov al,'0' ;yes - easier to just print it, then
- jmp chrout ; to eliminate all but the last zero.
- decout_nonzero:
-
- xor ax,ax ;start with all zeroes in al,bx,bp
- mov bx,ax
- mov bp,ax
-
- mov cx,32 ;32 bits in two 16 bit registers.
- decout_1:
- shl si,1
- rcl di,1
- xchg bp,ax
- call addbit
- xchg bp,ax
- xchg bx,ax
- call addbit
- xchg bx,ax
- adc al,al
- daa
- loop decout_1
-
- mov cl,'0' ;prepare to eliminate leading zeroes.
- call byteout ;output the first two.
- mov ax,bx ;output the next four
- call wordout ;output the next four
- mov ax,bp
- wordout:
- push ax
- mov al,ah
- call byteout
- pop ax
- byteout:
- mov ah,al
- shr al,1
- shr al,1
- shr al,1
- shr al,1
- call digout
- mov al,ah
- digout:
- and al,0fh
- add al,90h ;binary digit to ascii hex digit.
- daa
- adc al,40h
- daa
- cmp al,cl ;leading zero?
- je return
- mov cl,-1 ;no more leading zeros.
- chrout:
- push ax ;print the char in al.
- xchg al,dl
- mov ah,2
- int 21h
- xchg al,dl
- pop ax
- return:
- ret
-
-
- addbit: adc al,al
- daa
- xchg al,ah
- adc al,al
- daa
- xchg al,ah
- ret
-
- public memory_test
- memory_test:
- ;enter with ax = segment of memory to test, cx = number of bytes to test.
- ;exit with ne, bx->failing byte if the memory test failed.
- push ds
- mov ds,ax
- mov bx,-1
- memory_test_1:
- inc bx
- mov ah,ds:[bx] ;get a copy of the location.
- mov al,ah ;try to store the complement.
- not al
- mov ds:[bx],al
- cmp ds:[bx],al ;did the store work?
- mov ds:[bx],ah ;(in any case, restore the original)
- loope memory_test_1 ;keep going if the store worked.
- pop ds
- ret
-
- code ends
-
- end
-